Is there any way to separate infinite and finite lists?

后端 未结 5 1492
猫巷女王i
猫巷女王i 2020-12-16 23:25

For example, I am writing some function for lists and I want to use length function

foo :: [a] -> Bool
foo xs = length xs == 100

How can

相关标签:
5条回答
  • 2020-12-16 23:31

    There are a couple different ways to make a finite list type. The first is simply to make lists strict in their spines:

    data FList a = Nil | Cons a !(FList a)
    

    Unfortunately, this throws away all efficiency benefits of laziness. Some of these can be recovered by using length-indexed lists instead:

    {-# LANGUAGE GADTs #-}
    {-# LANGUAGE DataKinds #-}
    {-# LANGUAGE KindSignatures #-}
    {-# LANGUAGE ScopedTypeVariables #-}
    {-# OPTIONS_GHC -fwarn-incomplete-patterns #-}
    
    data Nat = Z | S Nat deriving (Show, Read, Eq, Ord)
    
    data Vec :: Nat -> * -> * where
      Nil :: Vec 'Z a
      Cons :: a -> Vec n a -> Vec ('S n) a
    
    instance Functor (Vec n) where
      fmap _f Nil = Nil
      fmap f (Cons x xs) = Cons (f x) (fmap f xs)
    
    data FList :: * -> * where
      FList :: Vec n a -> FList a
    
    instance Functor FList where
      fmap f (FList xs) = FList (fmap f xs)
    
    fcons :: a -> FList a -> FList a
    fcons x (FList xs) = FList (Cons x xs)
    
    funcons :: FList a -> Maybe (a, FList a)
    funcons (FList Nil) = Nothing
    funcons (FList (Cons x xs)) = Just (x, FList xs)
    
    -- Foldable and Traversable instances are straightforward
    -- as well, and in recent GHC versions, Foldable brings
    -- along a definition of length.
    

    GHC does not allow infinite types, so there's no way to build an infinite Vec and thus no way to build an infinite FList (1). However, an FList can be transformed and consumed somewhat lazily, with the cache and garbage collection benefits that entails.

    (1) Note that the type system forces fcons to be strict in its FList argument, so any attempt to tie a knot with FList will bottom out.

    0 讨论(0)
  • 2020-12-16 23:32

    ErikR and John Coleman have already answered the main parts of your question, however I'd like to point out something in addition:

    It's best to write your functions in a way that they simply don't depend on the finiteness or infinity of their inputs — sometimes it's impossible but a lot of the time it's just a matter of redesign. For example instead of computing the average of the entire list, you can compute a running average, which is itself a list; and this list will itself be infinite if the input list is infinite, and finite otherwise.

    avg :: [Double] -> [Double]
    avg = drop 1 . scanl f 0.0 . zip [0..]
      where f avg (n, i) = avg * (dbl n / dbl n') +
                           i            / dbl n'      where n'  = n+1
                                                            dbl = fromInteger
    

    in which case you could average an infinite list, not having to take its length:

    *Main> take 10 $ avg [1..]
    [1.0,1.5,2.0,2.5,3.0,3.5,4.0,4.5,5.0]
    

    In other words, one option is to design as much of your functions to simply not care about the infinity aspect, and delay the (full) evaluation of lists, and other (potentially infinite) data structures, to as late a phase in your program as possible.

    This way they will also be more reusable and composable — anything with fewer or more general assumptions about its inputs tends to be more composable; conversely, anything with more or more specific assumptions tends to be less composable and therefore less reusable.

    0 讨论(0)
  • 2020-12-16 23:34

    length traverses the entire list, but to determine if a list has a particular length n you only need to look at the first n elements.

    Your idea of using take will work. Alternatively you can write a lengthIs function like this:

    -- assume n >= 0
    lengthIs 0 [] = True
    lengthIs 0 _  = False
    lengthIs n [] = False
    lengthIs n (x:xs) = lengthIs (n-1) xs
    

    You can use the same idea to write the lengthIsAtLeast and lengthIsAtMost variants.

    0 讨论(0)
  • 2020-12-16 23:51

    On edit: I am primaily responding to the question in your title rather than the specifics of your particular example, (for which ErikR's answer is excellent).

    A great many functions (such as length itself) on lists only make sense for finite lists. If the function that you are writing only makes sense for finite lists, make that clear in the documentation (if it isn't obvious). There isn't any way to enforce the restriction since the Halting problem is unsolvable. There simply is no algorithm to determine ahead of time whether or not the comprehension

    takeWhile f [1..]
    

    (where f is a predicate on integers) produces a finite or an infinite list.

    0 讨论(0)
  • 2020-12-16 23:56

    Nats and laziness strike again:

    import Data.List
    
    data Nat = S Nat | Z deriving (Eq)
    
    instance Num Nat where
        fromInteger 0 = Z
        fromInteger n = S (fromInteger (n - 1))
    
        Z   + m = m
        S n + m = S (n + m)
    
    lazyLength :: [a] -> Nat
    lazyLength = genericLength
    
    main = do
        print $ lazyLength [1..]    == 100 -- False
        print $ lazyLength [1..100] == 100 -- True
    
    0 讨论(0)
提交回复
热议问题