Utils.purs 1.84 KB
Newer Older
1
module Gargantext.Utils where
2 3

import Prelude
4
import Data.Lens (Lens', lens)
5
import Data.Newtype (class Newtype, unwrap, wrap)
6 7
import Data.Set as Set
import Data.Set (Set)
8
import Data.String (length)
9

James Laver's avatar
James Laver committed
10 11 12 13
-- | Astonishingly, not in the prelude
id :: forall a. a -> a
id a = a

14 15 16 17 18 19
setterv :: forall nt record field.
           Newtype nt record
           => (record -> field -> record)
           -> field
           -> nt
           -> nt
20 21
setterv fn v t = (setter (flip fn v) t)

22 23 24 25 26
setter :: forall nt record.
          Newtype nt record
          => (record -> record)
          -> nt
          -> nt
27 28
setter fn = wrap <<< fn <<< unwrap

29 30 31 32 33
getter :: forall record field nt.
          Newtype nt record
          => (record -> field)
          -> nt
          -> field
34
getter fn = fn <<< unwrap
35 36 37 38 39 40

-- TODO: not optimal but Data.Set lacks some function (Set.alter)
toggleSet :: forall a. Ord a => a -> Set a -> Set a
toggleSet a s
  | Set.member a s = Set.delete a s
  | otherwise      = Set.insert a s
41 42 43 44 45 46 47

-- Default sort order is ascending, we may want descending
invertOrdering :: Ordering -> Ordering
invertOrdering LT = GT
invertOrdering GT = LT
invertOrdering EQ = EQ

48 49 50
csrfMiddlewareToken :: String
csrfMiddlewareToken = "Wy52D2nor8kC1r1Y4GrsrSIxQ2eqW8UwkdiQQshMoRwobzU4uldknRUhP0j4WcEM"

51 52 53
-- A lens that always returns unit
_unit :: forall s. Lens' s Unit
_unit = lens (\_ -> unit) (\s _ -> s)
54

55
glyphicon :: String -> String
56
glyphicon t = "btn glyphitem glyphicon glyphicon-" <> t
57

58 59 60
glyphiconActive :: String -> Boolean -> String
glyphiconActive icon b = glyphicon icon <> if b then " active" else ""

61 62 63 64 65 66 67 68
-- | Format a number with specified amount of zero-padding
zeroPad :: Int -> Int -> String
zeroPad pad num = zeros <> (show num)
  where
    numDigits = length $ show num
    zeros = if numDigits < pad then zeros' (pad - numDigits) else ""
    zeros' 0 = ""
    zeros' n = "0" <> (zeros' (n - 1))