Is there any way to separate infinite and finite lists?

后端 未结 5 1623
猫巷女王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.

提交回复
热议问题