Skip to content

Commit

Permalink
Merge pull request #5135 from etorreborre/etorreborre/fix/5134-print-…
Browse files Browse the repository at this point in the history
…error

fix: fix the textual representation of an ordinal number
  • Loading branch information
mergify[bot] committed Jun 26, 2024
2 parents 95fc3aa + 3556cb6 commit c10904c
Show file tree
Hide file tree
Showing 3 changed files with 43 additions and 9 deletions.
9 changes: 1 addition & 8 deletions parser-typechecker/src/Unison/PrintError.hs
Original file line number Diff line number Diff line change
Expand Up @@ -75,6 +75,7 @@ import Unison.Util.Monoid (intercalateMap)
import Unison.Util.Pretty (ColorText, Pretty)
import Unison.Util.Pretty qualified as Pr
import Unison.Util.Range (Range (..), startingLine)
import Unison.Util.Text (ordinal)
import Unison.Var (Var)
import Unison.Var qualified as Var

Expand Down Expand Up @@ -831,14 +832,6 @@ renderTypeError e env src = case e of
let sz = length wrongs
pl a b = if sz == 1 then a else b
in mconcat [txt pl, intercalateMap "\n" (renderSuggestion env) wrongs]
ordinal :: (IsString s) => Int -> s
ordinal n =
fromString $
show n ++ case last (show n) of
'1' -> "st"
'2' -> "nd"
'3' -> "rd"
_ -> "th"
debugNoteLoc a = if Settings.debugNoteLoc then a else mempty
debugSummary :: C.ErrorNote v loc -> Pretty ColorText
debugSummary note =
Expand Down
20 changes: 20 additions & 0 deletions parser-typechecker/src/Unison/Util/Text.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ module Unison.Util.Text where

import Data.Foldable (toList)
import Data.List (foldl', unfoldr)
import Data.List qualified as L
import Data.String (IsString (..))
import Data.Text qualified as T
import Data.Text.Encoding qualified as T
Expand Down Expand Up @@ -131,6 +132,25 @@ indexOf needle haystack =
needle' = toLazyText needle
haystack' = toLazyText haystack

-- | Return the ordinal representation of a number in English.
-- A number ending with '1' must finish with 'st'
-- A number ending with '2' must finish with 'nd'
-- A number ending with '3' must finish with 'rd'
-- _except_ for 11, 12, and 13 which must finish with 'th'
ordinal :: (IsString s) => Int -> s
ordinal n = do
let s = show n
fromString $ s ++
case L.drop (L.length s - 2) s of
['1', '1'] -> "th"
['1', '2'] -> "th"
['1', '3'] -> "th"
_ -> case last s of
'1' -> "st"
'2' -> "nd"
'3' -> "rd"
_ -> "th"

-- Drop with both a maximum size and a predicate. Yields actual number of
-- dropped characters.
--
Expand Down
23 changes: 22 additions & 1 deletion parser-typechecker/tests/Unison/Test/Util/Text.hs
Original file line number Diff line number Diff line change
Expand Up @@ -178,7 +178,28 @@ test =
)
(P.Join [P.Capture (P.Literal "zzzaaa"), P.Capture (P.Literal "!")])
in P.run p "zzzaaa!!!"
ok
ok,
scope "ordinal" do
expectEqual (Text.ordinal 1) ("1st" :: String)
expectEqual (Text.ordinal 2) ("2nd" :: String)
expectEqual (Text.ordinal 3) ("3rd" :: String)
expectEqual (Text.ordinal 4) ("4th" :: String)
expectEqual (Text.ordinal 5) ("5th" :: String)
expectEqual (Text.ordinal 10) ("10th" :: String)
expectEqual (Text.ordinal 11) ("11th" :: String)
expectEqual (Text.ordinal 12) ("12th" :: String)
expectEqual (Text.ordinal 13) ("13th" :: String)
expectEqual (Text.ordinal 14) ("14th" :: String)
expectEqual (Text.ordinal 21) ("21st" :: String)
expectEqual (Text.ordinal 22) ("22nd" :: String)
expectEqual (Text.ordinal 23) ("23rd" :: String)
expectEqual (Text.ordinal 24) ("24th" :: String)
expectEqual (Text.ordinal 111) ("111th" :: String)
expectEqual (Text.ordinal 112) ("112th" :: String)
expectEqual (Text.ordinal 113) ("113th" :: String)
expectEqual (Text.ordinal 121) ("121st" :: String)
expectEqual (Text.ordinal 122) ("122nd" :: String)
expectEqual (Text.ordinal 123) ("123rd" :: String)
]
where
log2 :: Int -> Int
Expand Down

0 comments on commit c10904c

Please sign in to comment.