Slightly optimize encoding of lists of known length (#1578)

This commit is contained in:
Simon Jakobi 2019-12-02 23:25:34 +01:00 committed by mergify[bot]
parent 96ae330fb5
commit 338d640dcc
2 changed files with 24 additions and 8 deletions

View File

@ -697,7 +697,8 @@ encodeExpressionInternal encodeEmbed = go
Encoding.encodeString "Sort"
a@App{} ->
encodeList
encodeListN
(2 + length arguments)
( Encoding.encodeInt 0
: go function
: map go arguments
@ -777,7 +778,8 @@ encodeExpressionInternal encodeEmbed = go
| null xs ->
encodeList2 (Encoding.encodeInt label) _T
| otherwise ->
encodeList
encodeListN
(2 + length xs)
( Encoding.encodeInt 4
: Encoding.encodeNull
: map go (Data.Foldable.toList xs)
@ -824,7 +826,8 @@ encodeExpressionInternal encodeEmbed = go
(Encoding.encodeString x)
Project t (Left xs) ->
encodeList
encodeListN
(2 + Dhall.Set.size xs)
( Encoding.encodeInt 10
: go t
: map Encoding.encodeString (Dhall.Set.toList xs)
@ -884,7 +887,8 @@ encodeExpressionInternal encodeEmbed = go
(Encoding.encodeString z)
TextLit (Chunks xys z) ->
encodeList
encodeListN
(2 + 2 * length xys)
( Encoding.encodeInt 18
: concatMap encodePair xys ++ [ Encoding.encodeString z ]
)
@ -900,7 +904,8 @@ encodeExpressionInternal encodeEmbed = go
encodeEmbed x
Let a b ->
encodeList
encodeListN
(2 + 3 * length as)
( Encoding.encodeInt 25
: concatMap encodeBinding (toList as) ++ [ go b ]
)
@ -966,9 +971,12 @@ encodeList4 :: Encoding -> Encoding -> Encoding -> Encoding -> Encoding
encodeList4 a b c d = Encoding.encodeListLen 4 <> a <> b <> c <> d
{-# INLINE encodeList4 #-}
encodeListN :: Int -> [ Encoding ] -> Encoding
encodeListN len xs = Encoding.encodeListLen (fromIntegral len) <> mconcat xs
{-# INLINE encodeListN #-}
encodeList :: [ Encoding ] -> Encoding
encodeList xs =
Encoding.encodeListLen (fromIntegral (length xs)) <> mconcat xs
encodeList xs = encodeListN (length xs) xs
{-# INLINE encodeList #-}
decodeImport :: Int -> Decoder s Import

View File

@ -21,6 +21,7 @@ module Dhall.Set (
, sort
, isSorted
, null
, size
) where
import Prelude hiding (null)
@ -64,7 +65,7 @@ instance Foldable Set where
null = Dhall.Set.null
{-# INLINABLE null #-}
length (Set s _) = Data.Set.size s
length = Dhall.Set.size
{-# INLINABLE length #-}
-- | Convert to an unordered @"Data.Set".`Data.Set.Set`@
@ -136,3 +137,10 @@ True
-}
null :: Set a -> Bool
null (Set s _) = Data.Set.null s
{-|
>>> size (fromList [1])
1
-}
size :: Set a -> Int
size (Set s _) = Data.Set.size s